home *** CD-ROM | disk | FTP | other *** search
Text File | 1990-09-14 | 44.7 KB | 1,359 lines | [TEXT/MPS ] |
- ; This is the source code to the Apple Video Driver. The specific-to-Apple Video card
- ;register manipulations have been removed; you should use whatever is appropriate for your card.
-
- ; This file is for information only, and is confidential. Do not distribute it. Questions should
- ; be directed to Mac Tech Support, “MacDTS” on either AppleLink or MCI Mail.
-
-
- ;
- ; File: TFBDriver.a
- ;
- ; To do: Does the save stuff in the dCtlStorage make sense?? Is it enough?
- ; If csMode = -1 on SetMode, then use mode, data in parameter RAM
- ; Need to return the mode on the reset call.
- ; *Allocate interrupt handler on open, deallocate on close, lock/unlock driver.
- ; Add 8-bit mode.
- ;
- ; SetMode needs to set the DCE dctlDevBase value (since a unique base is possible for each mode).
- ;
- ; Should VidReset initialize Gamma and Color tables?
- ;----------------------------------------------------------------
- ;
- ;
- ; Video Driver for TFB card.
- ;
- ; Written by EB 2-Jun-86
- ; Substantially modified by GN Sept-... 1986
- ;
- ;-----------------------------------------------------------------
-
-
- BLANKS ON
- STRING ASIS
- MACHINE MC68020
-
- LOAD 'inc.sum.d'
- LOAD 'nEqu.d'
- INCLUDE 'colorEqu.a'
- INCLUDE 'DepVideoEqu.a'
- INCLUDE 'IndVideoEqu.a'
- INCLUDE 'SlotIntEqu.a'
-
- VideoDrvr PROC EXPORT
- ;=====================================================================
- ; Local Vars, definitions, etc....
- ;=====================================================================
-
- ; This is device storage which is stored in the dCtlStorage field of the DCE.
-
- DCEPtr EQU 0 ; pointer to our DCE
- saveMode EQU DCEPtr+4 ; the current mode setting
- savePage EQU saveMode+2 ; the current page setting
- saveBaseAddr EQU savePage+2 ; the current base address
- saveSQElPtr EQU saveBaseAddr+4 ; the SQ element pointer (for _SIntRemove).
- GammaPtr EQU saveSQElPtr+4 ; the pointer to the Gamma correction table
- GFlags EQU GammaPtr+4 ; flags word
- VRAM256K EQU GFlags+2 ; boolean - TRUE if 256K vidRAM, FALSE if 512K
- dCtlSize EQU VRAM256K+2 ; size of dCtlStorage
-
- ; Flags within GFlags word
-
- GrayFlag EQU 15 ; luminance mapped if GFlags(GrayFlag) = 1
- IntDisFlag EQU 14 ; interrupts disabled if GFlags(IntFlag) =1
-
- TFB1K EQU 0
-
- ;=====================================================================
- ; Video Driver Header
- ;=====================================================================
-
-
- VidDrvr DC.W $4C00 ; ctl,status,needsLock
- DC.W 0,0,0 ; not an ornament
-
- ; Entry point offset table
-
- DC.W VideoOpen-VidDrvr ; open routine
- DC.W VidDrvr-VidDrvr ; no prime
- DC.W VideoCtl-VidDrvr ; control
- DC.W VideoStatus-VidDrvr ; status
- DC.W VideoClose-VidDrvr ; close
-
-
- STRING Pascal
- VideoTitle DC.B '.Display_Video_Apple_TFB' ;
- STRING ASIS
- ALIGN 2 ; make sure we're aligned
- DC.W 2 ; version-2
-
-
- ;
- **********************************************************************
- *
- * VideoOpen allocates private storage for the device in the DCE and locks
- * it down for perpituity. Also, install the interrupt handler and enable
- * the interrupts.
- * It also sets the default gamma table included in the driver
- *
- * Entry: A0 = param block pointer
- * A1 = DCE pointer
- *
- * Locals: A2 = Saved param block pointer
- * A3 = Saved DCE pointer
- * A4 = Saved interrupt handler ptr.
- *
- **********************************************************************
-
- ; Save registers
-
- ;+++ for MPW 2.0 AIncludes! WITH VDPageInfo,SlotIntQElement
- VideoOpen MOVE.L A0,A2 ;A2 <- param block pointer
- MOVE.L A1,A3 ;A3 <- DCE pointer
-
- ; Allocate private storage.
- MOVEQ #dCtlSize,D0 ; get size of parameters
- _ResrvMem ,SYS ; make room as low as possible
- MOVEQ #dCtlSize,D0 ; get size of parameters
- _NewHandle ,SYS,CLEAR ; get some memory for private storage
- BNE OpError ; => return an error in open
- MOVE.L A0,dCtlStorage(A3) ; save returned handle in DCE
- _HLock ; and lock it down
-
- ; Get and install the interrupt handler.
- LEA BeginIH,A4 ;Save Pointer to interrupt handler.
- MOVEQ #SQSize,D0 ;allocate a slot queue element
- _NewPtr ,SYS,CLEAR ;get it from system heap cleared
- BNE OpError
- MOVE.W #SIQType,SQType(A0) ;setup queue ID
- MOVE.L A4,SQAddr(A0) ;setup int routine address
- MOVE.L dctlDevBase(A3),SQParm(A0) ;save slot base addr as A3 parm
- CLR.L D0
- MOVE.B dctlSlot(A3),D0 ;setup slot #
- _SIntInstall ;and do install
- BNE.S OpError
-
-
- ; Save SQElPtr for removal.
- MOVE.L dCtlStorage(A3),A1 ;Get pointer to private storage
- MOVE.L (A1),A1 ;
- MOVE.L A0,saveSQElPtr(A1) ;Save the SQ element pointer.
-
- ; SO DRIVER DOESN'T CARRY REDUNDANT GAMMA TABLE, INITIALIZE DRIVER WITH LINEAR GAMMA TABLE.
- ; VALUES IN GAMMA TABLE ARE INVERTED SO WE DON'T NEED TO INVERT VALUES WE READ FROM IT.
-
- MOVEQ #0,D0 ; clear high word
- MOVE #256+GFormulaData,D0 ; get size of gamma table
- _NewPtr ,SYS,CLEAR ; allocate it in system heap
- BNE.S OpError ; =>failed! return error
-
- MOVE.L A0,GammaPtr(A1) ; else save off pointer
- CLR.L (A0)+ ; version = 0, type = 0
- MOVEQ #1,D0
- MOVE.L D0,(A0)+ ; formula size = 0, channel counte = 1
- MOVE.L #$01000008,(A0)+ ; 256 entries, 8 bits per entry
- MOVE #$FF,D0 ; get count for dbra loop
- @NxtEntry MOVE.B D0,(A0)+ ; set next byte
- DBRA D0,@NxtEntry ; repeat until done
-
- ; set luminance mapping and interrupts disabled to false
-
- CLR GFlags(A1) ; set all flags false
-
- ;
- ; size video RAM and save boolean in private storage
- ;
-
- MOVE.L dctlDevBase(A3),A0 ;get base of vRAM
- MOVE.L #TestPos,D1 ;get offset in D1
- MOVE.L #TestPat,(A0,D1.L) ;write to alleged RAM
- MOVE.L #-1,-(SP) ;write out some garbage to clear data lines
- CLR.L (SP)+ ;and pitch it
- MOVE.L (A0,D1.L),D0 ;read pattern back
- CMP.L #TestPat,D0 ;did it stick?
- SNE VRAM256K(A1) ;mark boolean (A1 still has private storage ptr)
-
- ; Enable interrupts.
-
- ADD.L #ClrVInt,A0 ;bump to interrupt reg
- CLR.B (A0) ;clear it.
-
- MOVEQ #0,D0 ;no error
- BRA.S EndOpen
-
-
- ; Error.
- OpError MOVE.L #OpenErr,D0 ; say can't open driver
-
-
- EndOpen RTS ;return
-
-
- **********************************************************************
- *
- * VideoClose releases the device's private storage.
- *
- *
- * Entry: A0 = param block pointer
- * A1 = DCE pointer
- *
- * Locals: A2 = Saved param block pointer
- * A3 = Saved DCE pointer
- * A4 = Temporary.
- *
- **********************************************************************
-
- VideoClose
- MOVE.L A0,A2 ;A2 <- param block pointer
- MOVE.L A1,A3 ;A3 <- DCE pointer
-
- MOVE.L dCtlDevBase(A3),A4 ;A4 <- base address of device.
- ADD.L #DisableVInt,A4 ;Adjust the base
- CLR.B (A4) ;Disable interrupt from card
-
- MOVE.L dCtlStorage(A3),A0 ;Get pointer to private storage
- MOVE.L (A0),A0 ;
- MOVE.L saveSQElPtr(A0),A0 ;Get the SQ element pointer.
- MOVE.B dCtlSlot(A3),D0 ;get the slot of the interrupt handler
- _SIntRemove ;Remove the interrupt handler.
-
- MOVE.L dCtlStorage(A3),A0 ;Get pointer to private storage
- MOVE.L (A0),A0 ;
- MOVE.L GammaPtr(A0),A0 ;get pointer to gamma table
- _DisposPtr ;and dispose it
-
- MOVE.L dCtlStorage(A3),A0 ;Dispose of the private storage.
- _DisposHandle ;
-
-
- MOVEQ #0,D0 ;get error into D0
- RTS ;return to caller
-
- ;
- **********************************************************************
- *
- * Video Driver Control Call Handler. Right now there are six calls:
- *
- * (0) Reset (VAR mode, page: INTEGER; VAR BaseAddr: Ptr);
- * (1) KillIO
- * (2) SetMode(mode, page: INTEGER; VAR BaseAddr: Ptr);
- * (3) SetEntries ( Table: Ptr; Start,Count : integer );
- * (4) SetGamma ( Table : Ptr );
- * (5) GrayPage (page);
- * (6) SetGray (csMode = 0 for color, 1 for gray)
- * (7) SetInterrupt (csMode = 0 to disable, 1 to enable)
- *
- * Entry: A0 = param block pointer
- * A1 = DCE pointer
- * Uses: A2 = cs parameters (ie. A2 <- csParam(A0)) (must be preserved)
- * A3 = scratch (doesn't need to be preserved)
- * A4 = scratch (must be preserved)
- * D0-D3 = scratch (don't need to be preserved)
- *
- * Exit: D0 = error code
- *
- **********************************************************************
-
- ; Decode the call
- VideoCtl MOVEM.L A0/A4/D4,-(SP) ; save work registers (A0 is saved because it is used by ExitDrvr).
-
- MOVE.W csCode(A0),D0 ; get the opCode
- MOVE.L csParam(A0),A2 ; A2 <- Ptr to control parameters
-
- CMP.W #7,D0 ;IF csCode NOT IN [0..7] THEN
- BHI.S CtlBad ; Error, csCode out of bounds.
- LSL.W #1,D0 ;Adjust csCode to be an index into the table.
- MOVE.W CtlJumpTbl(PC,D0.W),D0 ;Get the relative offset to the routine.
- JMP CtlJumpTbl(PC,D0.W) ;GOTO the proper routine.
-
- CtlJumpTbl DC.W VidReset-CtlJumpTbl ;$00 => VidReset
- DC.W CtlGood-CtlJumpTbl ;$01 => CtlGood
- DC.W SetVidMode-CtlJumpTbl ;$02 => SetVidMode
- DC.W SetEntries-CtlJumpTbl ;$03 => SetEntries
- DC.W SetGamma-CtlJumpTbl ;$04 => SetGamma
- DC.W GrayPage-CtlJumpTbl ;$05 => GrayPage
- DC.W SetGray-CtlJumpTbl ;$06 => SetGray
- DC.W SetInterrupt-CtlJumpTbl ;$07 => SetInterrupt
-
- SENoMem ADDQ #4,SP ; fix up the stack
- CtlBad MOVEQ #controlErr,D0 ; else say we don't do this one
- BRA.S CtlDone ; and return
-
- CtlGood MOVEQ #noErr,D0 ; return no error
-
- CtlDone MOVEM.L (SP)+,A0/A4/D4 ; restore registers.
- BRA ExitDrvr
-
-
-
- VidReset
- ;---------------------------------------------------------------------
- ;
- ; Reset the card to its default (one bit per pixel)
- ;
- ;---------------------------------------------------------------------
-
- BSR TFBInit ; initialize the card
- MOVE #OneBitMode,csMode(A2) ; return default mode
- MOVE #1,D1 ; get depth in D1
- MOVEQ #0,D0 ; get page in D0
- MOVE D0,csPage(A2) ; return the page
- MOVE.L dCtlStorage(A1),A3 ; get handle to our data
- MOVE.L (A3),A3 ; A3 = our data
- BSR TFBSetDepth ; set the depth from D1
- BSR TFBSetPage ; set the page from D0
- MOVE.L saveBaseAddr(A3),csBaseAddr(A2) ; return the base address
- BSR GrayScreen ; paint the screen gray
- BRA.S CtlGood ; => no error
-
-
-
- SetVidMode
- ;---------------------------------------------------------------------
- ;
- ; Set the card to the specified mode and page.
- ; If either is invalid, returns badMode error.
- ;
- ; If the card is already set to the specified mode, then do nothing.
- ;
- ; Note: Mode set is [1,2,4,8].
- ;
- ;---------------------------------------------------------------------
-
- MOVE.W csMode(A2),D1 ; D1 = mode
- BSR ChkMode ; get mode, check, map to depth (1, 2, 4 or 8) {D1 <- depth}
- BNE.S CtlBad ; => not a valid mode
-
- MOVE.W csPage(A2),D0 ; D0 = page
- BSR ChkPage ; check page
- BNE.S CtlBad ; => not a valid page
-
- ; Only set the mode if it has changed
- ; TFBSetDepth and TFBSetPage update the saved data in the dCtlStorage
-
- SetEm
- MOVE.L dCtlStorage(A1),A3 ; get handle to our data
- MOVE.L (A3),A3 ; A3 = our data
- MOVE.W csMode(A2),D2 ; D2 = mode
- CMP saveMode(A3),D2 ; has the mode changed?
- BEQ.S ModeOK1 ; => no, check the page
- BSR GrayTable ; set color table to gray
- BSR TFBSetDepth ; set the depth, get rowbytes
- BSR TFBSetPage ; set the page
- BRA.S NoChange ; => and return
-
- ModeOK1 BSR TFBSetPage ; set the page
-
- NoChange MOVE.L saveBaseAddr(A3),csBaseAddr(A2) ; return the base address
- BRA.S CtlGood ; => return no error
-
-
- GrayTable ; new routine
- ;---------------------------------------------------------------------
- ;
- ; Jam the entire color table to gray before switching modes.
- ;
- ;---------------------------------------------------------------------
- MOVEM.L A0-A1/D0-D1,-(SP) ; save registers
- MOVE SR,-(SP) ; preserve status register
- MOVE.W #$2200,SR ; disable cursor interrupts
- BSR WaitVSync ; wait for next blanking period
-
- MOVE.L dCtlStorage(A1),A0 ; get handle to private storage
- MOVE.L (A0),A0 ; get pointer to storage (it's locked!)
- MOVE.L GammaPtr(A0),A0 ; get pointer to gamma data structure
- MOVE GFormulaSize(A0),D0 ; get the size of formula data
- LEA GFormulaData(A0),A0 ; point to formula data
- ADD D0,A0 ; first correction table starts here
- MOVE #$80,D1 ; get value for medium gray
- MOVE.B (A0,D1),D1 ; get inverted, corrected gray
-
- MOVE.L dCtlDevBase(A1),A0 ; A0 <- base address of device.
- ADD.L #ClrTbl+wCLUTDataReg,A0 ; add offset to color table data register
- MOVE #$FF,D0 ; get count
- @Repeat MOVE.B D1,(A0) ; PUT RED COMPONENT
- MOVE.B D1,(A0) ; PUT GREEN COMPONENT
- MOVE.B D1,(A0) ; PUT BLUE COMPONENT
- DBRA D0,@Repeat ; UNTIL (entire table has been copied)
- MOVE (SP)+,SR ; restore the status reg
- MOVEM.L (SP)+,A0-A1/D0-D1 ; restore saved registers
- RTS
-
-
- SetEntries
- ;---------------------------------------------------------------------
- ;
- ; Input :
- ; csParam -> datablock
- ; datablock = csTable -> table of colorSpecs (not colortable)
- ; csStart -> where to start setting, or -1
- ; csCount -> # of entries to change
- ;
- ; This call has two modes. In SEQUENCE mode, csCount entries are changed
- ; in the CLUT, starting at csStart. In INDEX mode, csCount entries are
- ; installed into the CLUT at the positions specified by their .value fields.
- ; This mode is selected by passing csStart = -1. In both cases, entries are
- ; range-checked to the dynamic range of the video mode (bits/pixel).
- ;
- ;---------------------------------------------------------------------
- ;
- ; Set the CLUT.
- ; A0 = Ptr to the table.
- ; A1 = Ptr to DCE.
- ; A2 = Ptr to cs parameter record.
- ; A3 = Ptr to Vert sync state or Ptr to CLUT
- ; A4 = Ptr to gamma red table
- ; A5 = Ptr to gamma green table
- ; A6 = Ptr to gamma blue table
- ;
- ; D0-D4 = Scratch
- ; D5 = GRAY FLAG
- ; D6 = Index range [0..n].
- ; D7 = Shift constant (7,6,4 or 0).
- ;
- ;---------------------------------------------------------------------
-
- ; Initialize loop.
- MOVE.L csTable(A2),D0 ; Check for a nil pointer.
- BEQ.S CtlBad
-
- MOVEM.L A5-A6/D5-D7,-(SP) ; save registers for gamma (A4/D4 saved by VideoCtl)
- MOVE.L dCtlStorage(A1),A0 ; get handle to private storage
- MOVE.L (A0),A0 ; get pointer to storage (it's locked!)
- MOVE GFLAGS(A0),D5 ; KEEP FLAGS WORD IN D5
- MOVE.L GammaPtr(A0),A0 ; get pointer to gamma data structure
- MOVE.W GFormulaSize(A0),D0 ; get the size of formula data
- LEA GFormulaData(A0),A4 ; point to formula data
- ADD D0,A4 ; red correction table starts here
- MOVE.L A4,A5 ; get default pointer to green data
- MOVE.L A4,A6 ; get default pointer to blue data
- CMP #1,GChanCnt(A0) ; if only only one table, we're set
- BEQ.S OneTbl ; => just one table
-
- MOVE GDataCnt(A0),D0 ; get # entries in table
- MOVE GDataWidth(A0),D1 ; get width of each entry in bits
- ADD #7,D1 ; round to nearest byte
- LSR #3,D1 ; get bytes per entry
- MULU D1,D0 ; get size of table in bytes
-
- ADDA D0,A5 ; calc base of green
- ADDA D0,A6 ; calc base of blue
- ADDA D0,A6 ; calc base of blue
-
- OneTbl SUB #16*8,SP ; make room for 16 entries
-
- ; Get the index range (D6) and the shift constant (D7).
-
- BSR CvtIndex
- MOVE.L csTable(A2),A0 ; get colorSpec pointer in A0
-
- ; If it is sequence mode, then go do fast way
-
- MOVE.W csStart(A2),D1 ; D1 = mode/start
- BMI.S NoSequence ; => not sequential
- CMP #255,D6 ; doing 256 entries?
- BNE.S SLOSEQUENCE ; =>NO, NOT 8 BIT MODE
- CMP #4,csCount(A2) ; MORE THAN 4 ENTRIES?
- BGT SEQUENCE ; =>yes, fast special case
-
- ; For 4-bit and less, set up a color table on the stack that has indices
-
- SloSequence MOVE.L SP,A3 ; point to stackSpecs
- MOVE csCount(A2),D0 ; get elements to copy
-
- @NxtSpec MOVE D1,(A3)+ ; copy index into stackSpec
- MOVE.L (A0)+,D2 ; get index, red
- MOVE D2,(A3)+ ; copy red
- MOVE.L (A0)+,(A3)+ ; copy green, blue
- ADDQ #1,D1 ; bump to next index
- DBRA D0,@NxtSpec ; => repeat for all specs
-
- MOVE.L SP,A0 ; get colorSpec pointer in A0
-
- ; disable cursor interrupts so that there will be time to change colors
- ; A0 already contains the pointer to colorSpecs
-
- NoSequence MOVE SR,-(SP) ; set disable interrupt disable up to level 2
- MOVE.W #$2200,SR ;
-
- BSR WaitVSync ; wait for next blanking period (preserves A0)
-
- ; Copy the table to the CLUT
-
- MOVE.W csCount(A2),D0 ; get the number of elements to change
-
- @Repeat MOVE.L (A0)+,D2 ; GET INDEX, RED
- SWAP D2 ; GET INDEX
- MOVEQ #-1,D1 ; SET HIGH BITS FOR ROL.L
- MOVE D2,D1 ; AND MOVE INTO D1
- CMP.W D6,D1 ; IF D1 > MAXINDEX THEN
- BHI.S @Until ; INDEX OUT OF RANGE
-
- SWAP D2 ; LEAVE RED IN D2
- MOVE.L (A0)+,D3 ; GET GREEN,BLUE
- MOVE.L D3,D4 ; GET BLUE IN D4.W
- SWAP D3 ; GET GREEN IN D3.W
- TST D5 ; TEST FLAGS WORD
- BPL.S @NOGRAY ; =>DON'T DO LUMINANCE MAPPING
-
- MULU #$4CCC,D2 ; MULTIPLY BY WEIGHT FOR RED
- MULU #$970A,D3 ; MULTIPLY BY WEIGHT FOR GREEN
- MULU #$1C28,D4 ; MULTIPLY BY WEIGHT FOR BLUE
- ADD.L D3,D2 ; GET SUM OF RED, GREEN
- ADD.L D4,D2 ; AND BLUE INTO D2
- ROL.L #8,D2 ; GET HIGH BYTE AS LUMINANCE
- AND #$00FF,D2 ; MAKE D2 A BYTE INDEX
- MOVE.B (A4,D2),D2 ; GET GAMMA CORRECTED GRAY
- ; Put value in D2 to all three components on video card
- DBRA D0,@Repeat ; UNTIL (entire table has been copied)
- BRA.S @NOMORE ; => RETURN
-
- @NOGRAY ROR #8,D2 ; GET HIGH BYTE OF RED
- MOVEQ #0,D1 ; CLEAR OUT INDEX
- MOVE.B D2,D1 ; AND GET BYTE INDEX
- MOVE.B (A4,D1),D1 ; GET INVERTED, CORRECTED RED
- ; Put red value to color table on card
-
- ROR #8,D3 ; GET HIGH BYTE OF GREEN
- MOVEQ #0,D1 ; CLEAR OUT INDEX
- MOVE.B D3,D1 ; AND GET BYTE INDEX
- MOVE.B (A5,D1),D1 ; GET INVERTED, CORRECTED GREEN
- ; Put green value to color table on card
-
- ROR #8,D4 ; GET HIGH BYTE OF BLUE
- MOVEQ #0,D1 ; CLEAR OUT INDEX
- MOVE.B D4,D1 ; AND GET BYTE INDEX
- MOVE.B (A6,D1),D1 ; GET INVERTED, CORRECTED BLUE
- ; Put blue value to color table on card
-
- @Until DBRA D0,@Repeat ; UNTIL (entire table has been copied)
-
- @NOMORE MOVE.W (SP)+,SR ; restore the status reg
- ADD #16*8,SP ; strip stackSpecs
- MOVEM.L (SP)+,A5/A6/D5-D7 ; restore saved registers
-
- BRA CtlGood ; => return no error
-
- SEQUENCE
-
- ; make sure the stack is long aligned, and allocate buffer on stack
-
- MOVE.L SP,D1 ; get stack
- MOVE.L D1,D0 ; copy stack
- NEG D0 ; get amount to subtract
- AND #$3,D0 ; get low bits
- BEQ.S StkOk ; => already long aligned
- SUB D0,SP ; else make stack long aligned
- StkOk MOVE.L D1,-(SP) ; save original stack on stack
-
- _StackSpace ; how much room is left on stack?
- CMP.L #$400+$100,D0 ; enough for 1024+256 slop?
- BLT SENoMem ; sorry, not enough
-
- SUB #$400,SP ; make room for 256*4 bytes
-
- ; build the color table on the stack
-
- MOVE csStart(A2),D1 ; get the starting element
- LEA 0(SP,D1*4),A3 ; A3 = pointer to first stack element
- MOVE.W csCount(A2),D0 ; get the number of elements to change
- MOVE.L csTable(A2),A0 ; get a pointer to the table of colorspecs
-
- @Repeat CMP D6,D1 ; check index against max
- BGT.S NoMore ; => oops, table is full
-
- TST D5 ; TEST FLAGS WORD
- BPL.S @NOGRAY ; =>DON'T DO LUMINANCE MAPPING
-
- MOVE.L (A0)+,D2 ; GET RED IN D2.W
- MOVE.W (A0)+,D3 ; GET GREEN IN D3.W
- MOVE.W (A0)+,D4 ; GET BLUE IN D4.W
-
- MULU #$4CCC,D2 ; MULTIPLY BY WEIGHT FOR RED
- MULU #$970A,D3 ; MULTIPLY BY WEIGHT FOR GREEN
- MULU #$1C28,D4 ; MULTIPLY BY WEIGHT FOR BLUE
- ADD.L D3,D2 ; GET SUM OF RED, GREEN
- ADD.L D4,D2 ; AND BLUE INTO D2
- ROL.L #8,D2 ; GET HIGH BYTE AS LUMINANCE
- MOVEQ #0,D3 ; CLEAR HIGH PART
- MOVE.B D2,D3 ; GET THE CORRECTED BLUE
- MOVE.B (A4,D3),D2 ; GET INVERTED, GAMMA CORRECTED GRAY
-
- MOVE.B D2,D3 ; GET THE CORRECTED BLUE
- LSL.L #8,D3 ; D3 = 00B0
- MOVE.B D2,D3 ; D3 = 00BG
- LSL.L #8,D3 ; D3 = 0BG0
- MOVE.B D2,D3 ; D3 = 0BGR
- MOVE.L D3,(A3)+ ; put blue, green, red to stack
- ADDQ #1,D1 ; bump index
- DBRA D0,@Repeat ; UNTIL (entire table has been copied)
- BRA.S NOMORE ; => RETURN
-
- @NOGRAY MOVEQ #0,D2 ; clear high part
- MOVE.B rgb+blue(A0),D2 ; get blue
- MOVE.B (A4,D2),D3 ; get the gamma corrected blue
- LSL.L #8,D3 ; D3 = xxBx
- MOVE.B rgb+green(A0),D2 ; get green
- MOVE.B (A5,D2),D3 ; get the gamma corrected green
- LSL.L #8,D3 ; D3 = xBGx
- MOVE.B rgb+red(A0),D2 ; get red
- MOVE.B (A6,D2),D3 ; get the gamma corrected red (D3 = xBGR)
- MOVE.L D3,(A3)+ ; put blue, green, red to stack
-
- ADDQ #1,D1 ; bump index
- ADDQ #8,A0 ; point to next color spec
- @Until DBRA D0,@Repeat ; UNTIL (entire table has been copied)
-
- NoMore MOVE.W SR,-(SP) ; set disable interrupt disable up to level 2
- MOVE.W #$2200,SR ;
- MOVE.L A3,A0 ; save pointer to last element inserted
-
- BSR WaitVSync ; wait for vertical blanking
-
- MOVEQ #0,D1 ; clear out D1
- MOVE.B csStart+1(A2),D1 ; get the starting element to change
- NOT.B D1 ; negate for position of starting element
- MOVE.W csCount(A2),D0 ; get the number of elements to change
- SUB.W D0,D1 ; calc first element to change
- NOT.B D1 ; and negate for nubus
-
- NextRGB MOVE.L -(A0),D1 ; get B,G,R
- ; set red
- LSR.L #8,D1 ; get green
- ; set green
- LSR.L #8,D1 ; get blue
- ; set green
- DBRA D0,NextRGB ; => repeat for next RGB
-
- MOVE.W (SP)+,SR ; restore the status reg
- ADD #$400,SP ; strip stack frame
- MOVE.L (SP)+,SP ; restore stack alignment
- ADD #16*8,SP ;
- MOVEM.L (SP)+,A5/A6/D5-D7 ; restore saved registers
-
- BRA CtlGood ; => return no error
-
-
- SetGamma ; <C522/15Dec86> DAF
- ;---------------------------------------------------------------------
- ;
- ; Set the gamma table
- ; A0 = Ptr to private storage
- ; A1 = Ptr to DCE
- ; A2 = Ptr to cs parameter record
- ;
- ;---------------------------------------------------------------------
-
- ; get new gamma table and check that we know how to handle it
-
- MOVE.L A1,-(SP) ; save DCE pointer
- MOVE.L dCtlStorage(A1),A3 ; get handle to private storage
- MOVE.L (A3),A3 ; get pointer to storage
-
- MOVE.L csGTable(A2),D0 ; test for a NIL pointer
- BEQ @BadCtl ; if so, then bad result
- MOVE.L D0,A1 ; get pointer to new gamma table
-
- TST.L GVersion(A1) ; version, type = 0?
- BNE @BadCtl ; => no, return error
- CMP #8,GDataWidth(A1) ; is data width 8?
- BNE @BadCtl ; => no, return error
- CMP #256,GDataCnt(A1) ; 256 values per channel?
- BNE.S @BadCtl ; => no, return error
-
- ; if new table is different size, reallocate memory
-
- MOVE.L GammaPtr(A3),A0 ; get current gamma in A0
- MOVE GFormulaSize(A1),D0 ; get size of formula in new
- CMP GFormulaSize(A0),D0 ; same as current gamma table
- BNE.S @GetNew ; =>no, resize pointer
- MOVE GChanCnt(A1),D0 ; get number of tables in new
- CMP GChanCnt(A0),D0 ; same as current gamma table?
- BEQ.S @SizeOK ; => yes, data size ok
- BGT.S @GetNew ; => new one is bigger, save old one
- @NewSize _DisposPtr ; if new one smaller, dispose old one
- CLR.L GammaPtr(A3) ; flag it's been disposed
-
- @GetNew MOVE #256,D0 ; get number of entries
- MULU GChanCnt(A1),D0 ; multiply by number of tables
- ADD GFormulaSize(A1),D0 ; add size of formula data
- ADD #GFormulaData,D0 ; add gamma table header size
- _NewPtr ,Sys ; and allocate a new pointer
- BNE.S @BadCtl ; => unable to allocate storage
-
- MOVE.L GammaPtr(A3),D0 ; get old gamma table
- MOVE.L A0,GammaPtr(A3) ; save new gamma table
- TST.L D0 ; was there an old one?
- BEQ.S @SizeOK ; => no, already disposed
- MOVE.L D0,A0 ; else get old table
- _DisposPtr ; and dispose of old gamma table
-
- MOVE.L GammaPtr(A3),A0 ; get new gamma table back
-
- ; copy the gamma table header
-
- @SizeOK MOVE GChanCnt(A1),D0 ; get number of tables
- MOVE GFormulaSize(A1),D1 ; get size of formula data
- MOVE.L (A1)+,(A0)+ ; copy gamma header
- MOVE.L (A1)+,(A0)+ ; which is
- MOVE.L (A1)+,(A0)+ ; 12 bytes long ***
-
- ; copy the data, inverted for nubus
-
- MOVE #256,D2 ; get number of entries
- MULU D0,D2 ; multiply by number of tables
- ADD D1,D2 ; add in size of formula data
- SUBQ #1,D2 ; get count - 1
- @NxtByte MOVE.B (A1)+,D0 ; get a byte
- NOT.B D0 ; invert it for nubus
- MOVE.B D0,(A0)+ ; move a byte
- DBRA D2,@NxtByte ; => repeat for all bytes
-
- MOVE.L (SP)+,A1 ; restore DCE pointer
- BRA CtlGood ; => return no error
-
- @BadCtl MOVE.L (SP)+,A1 ; restore DCE pointer
- BRA CtlBad ; => return an error
-
-
-
-
- GrayPage ; <EHB12/16>
- ;---------------------------------------------------------------------
- ;
- ; Clear the specified page in the current mode to gray
- ;
- ; A0 = Ptr to private storage
- ; A1 = Ptr to DCE
- ; A2 = Ptr to cs parameter record
- ;
- ;---------------------------------------------------------------------
-
- MOVE.L dCtlStorage(A1),A3 ; get handle to our storage
- MOVE.L (A3),A3 ; get pointer to our storage
- MOVE saveMode(A3),D1 ; D1 = mode
- BSR ChkMode ; convert mode to depth in D1
- BNE CtlBad ; => not a valid depth
-
- MOVE csPage(A2),D0 ; D0 = page
- BSR ChkPage ; check page
- BNE CtlBad ; => not a valid page
-
- BSR GrayScreen ; paint the screen gray
-
- BRA CtlGood ; => return no error
-
-
- SetGray
- ;---------------------------------------------------------------------
- ;
- ; Set luminance mapping on (csMode = 1) or off (csMode = 0)
- ;
- ; When luminance mapping is on, RGB values passed to setEntries are mapped
- ; to grayscale equivalents before they are written to the CLUT.
- ;
- ; A0 = Ptr to private storage
- ; A1 = Ptr to DCE
- ; A2 = Ptr to cs parameter record
- ;
- ;---------------------------------------------------------------------
-
- MOVE.L dCtlStorage(A1),A3 ; get handle to our storage
- MOVE.L (A3),A3 ; get pointer to our storage
- MOVE GFlags(A3),D0 ; get current flags word
- MOVE.B csMode(A2),D1 ; get boolean
- BFINS D1,D0{16:1} ; set grayFlag
- MOVE D0,GDFlags(A3)
- BRA CtlGood ; => return no error
-
-
- SetInterrupt
- ;---------------------------------------------------------------------
- ;
- ; Enable (csMode = 0) or disable (csMode = 1) VBL interrupts
- ;
- ; As a future performance enhancement, interrupts on the card can be
- ; disabled or enabled from software. For instance, if the cursor is
- ; not on a screen, and there is nothing in the Slot Interrupt Queue
- ; for that device, interrupts may be disabled reducing interrupt
- ; overhead for the system.
- ;
- ; A0 = Ptr to private storage
- ; A1 = Ptr to DCE
- ; A2 = Ptr to cs parameter record
- ;
- ;---------------------------------------------------------------------
-
- ;+++ for MPW 2.0 AIncludes! WITH VDPageInfo,SlotIntQElement
-
- MOVE.L dCtlStorage(A1),A3 ; get handle to our storage
- MOVE.L (A3),A3 ; get pointer to our storage
- MOVE GFlags(A3),D0 ; get current flags word
- MOVE.B csMode(A2),D1 ; get boolean
- BFINS D1,D0{17:1} ; set IntFlag
- MOVE D0,GDFlags(A3) ; put flag word back
-
- BTST #IntDisFlag,D0 ; is the flag on or off?
- BEQ.S EnableThem ; if zero, then enable
-
- ; this code disables VBL interrupts, then removes the interrupt handler
-
- BSR WaitVSync ; to be safe, wait for the next VBL
- MOVE.L dCtlDevBase(A1),A1 ; get the device base
- ADD.L #DisableVInt,A1 ; point to hardware register
- CLR.B (A1) ; hit the register
-
- MOVE.L saveSQElPtr(A0),A0 ; get the SQ element pointer
- _SIntRemove ; remove the interrupt handler
- BRA CtlGood ; done
-
- EnableThem
- MOVE.L A0,A2 ; save private pointer
- LEA BeginIH,A4 ; save Pointer to interrupt handler
- MOVEQ #SQSize,D0 ; allocate a slot queue element
- _NewPtr ,SYS,CLEAR ; get it from system heap cleared
- BNE CtlBad ; if not allocated, return bad
- MOVE.W #SIQType,SQType(A0) ; setup queue ID
- MOVE.L A4,SQAddr(A0) ; setup int routine address
- MOVE.L dctlDevBase(A1),SQParm(A0) ; save slot base addr as A3 parm
- CLR.L D0
- MOVE.B dctlSlot(A1),D0 ; setup slot #
- _SIntInstall ; and do install
- BNE CtlBad
-
- MOVE.L A0,saveSQElPtr(A2) ; save the queue element for eventual disposal
- MOVE.L dctlDevBase(A1),A0 ; get hardware base
- ADD.L #ClrVInt,A0 ; hit the clear register (which also enables)
- CLR.B (A0) ; start interrupts happening
-
- BRA CtlGood ; and go home
- ;+++ ENDWITH
-
- ;
- **********************************************************************
- *
- * Video Driver Status Call Handler. Right now there are eight calls:
- *
- * (0) Error
- * (1) Error
- * (2) GetMode
- * (3) GetEntries
- * (4) GetPage
- * (5) GetPageBase
- * (6) GetGray
- * (7) GetInterrupt
- * (8) GetGamma
- *
- * Entry: A0 = param block
- * A1 = DCE pointer
- * Uses: A2 = cs parameters (ie. A2 <- csParam(A0)) (must be preserved)
- * A3 = scratch (doesn't need to be preserved)
- * D0-D3 = scratch (don't need to be preserved)
- *
- * Exit: D0 = error code
- *
- **********************************************************************
-
- VideoStatus
- MOVE.L A0,-(SP) ; save a register
- MOVE.W csCode(A0),D0 ; get the opCode
- MOVE.L csParam(A0),A2 ; A2 <- Ptr to control parameters
-
-
- CMP.W #6,D0 ;IF csCode NOT IN [0..6] THEN
- BHI.S StatBad ; Error, csCode out of bounds.
- LSL.W #1,D0 ;Adjust csCode to be an index into the table.
- MOVE.W StatJumpTbl(PC,D0.W),D0 ;Get the relative offset to the routine.
- JMP StatJumpTbl(PC,D0.W) ;GOTO the proper routine.
-
- StatJumpTbl DC.W StatBad-StatJumpTbl ;$00 => Error
- DC.W StatBad-StatJumpTbl ;$01 => Error
- DC.W GetMode-StatJumpTbl ;$02 => GetMode
- DC.W GetEntries-StatJumpTbl ;$03 => GetEntries {NOT YET}
- DC.W GetPage-StatJumpTbl ;$04 => GetPage
- DC.W GetPageBase-StatJumpTbl ;$05 => GetPageBase
- DC.W GetGray-StatJumpTbl ;$06 => GetGray
- DC.W GetInterrupt-StatJumpTbl ;$07 => GetInterrupt
- DC.W GetGamma-StatJumpTbl ;$08 => GetGamma
-
- StatBad MOVEQ #statusErr,D0 ; else say we don't do this one
- BRA StatDone ; and return
-
- StatGood MOVEQ #noErr,D0 ; return no error
-
- StatDone MOVE.L (SP)+,A0 ; restore saved register
- BRA ExitDrvr
-
-
- GetMode
- ;---------------------------------------------------------------------
- ;
- ; Return the current mode
- ;
- ;---------------------------------------------------------------------
-
- MOVE.L dCtlStorage(A1),A3 ; get handle to our storage
- MOVE.L (A3),A3 ; get pointer to our storage
- MOVE.W saveMode(A3),csMode(A2) ; return the mode
- MOVE.W savePage(A3),csPage(A2) ; return the page number
- MOVE.L saveBaseAddr(A3),csBaseAddr(A2) ; and the base address
-
- BRA.S StatGood ; => return no error
-
-
- GetEntries
- ;---------------------------------------------------------------------
- ;
- ; Get the CLUT.
- ;
- ;---------------------------------------------------------------------
-
- ; Initialize loop.
- MOVE.L csTable(A2),D0 ; Check for a nil pointer.
- BEQ.S StatBad
- MOVE.L D0,A0 ; A0 <- pointer to table.
-
- CMP.W #-1,csStart(A2) ; is it index or sequence mode?
- BEQ.S GECom ; if index, then continue
-
- MOVE.W csCount(A2),D0 ; get the count
- MOVE.W D0,D1 ; make a copy for index loop
- MOVE.W D0,D2 ; make a copy of the count
- ADD.W csStart(A2),D2 ; get last index
- @1
- MOVE.W D2,value(A0,D1*8) ; write the index into the table
- SUBQ #1,D2 ; decrease index
- DBRA D1,@1 ; for all indices
-
- GECom
-
- MOVEM.L D6-D7,-(SP) ; SAVE WORK REGISTERS
-
- ; Get the index range (D6) and the shift constant (D7).
- BSR CvtIndex
-
- ; Copy the CLUT to the Table
-
- ; REPEAT
- @Repeat MOVE.W value(A0),D1 ; D1 <- xindex.
- CMP.W D6,D1 ; IF D1 > D6 THEN
- BHI.S @Until ; GOTO @Until {Index is out of range for this mode}
-
- OR.L #$FFFF0000,D1 ; get ones in hi half of d1.<C389/10Nov86>
- ROL.L D7,D1 ; shift it. <C389/10Nov86>
-
- ; Get red into D1
- NOT.W D1
- MOVE.B D1,rgb+red(A0)
- MOVE.B D1,rgb+red+1(A0) ; <C715>
-
- ; Get green into D1
- NOT.W D1
- MOVE.B D1,rgb+green(A0)
- MOVE.B D1,rgb+green+1(A0) ; <C715>
-
- ; Get blue into D1
- NOT.W D1
- MOVE.B D1,rgb+blue(A0)
- MOVE.B D1,rgb+blue+1(A0) ; <C715>
-
- @Until ADDQ.L #cSpecRec,A0 ; A0 <- next entry in the table.
- DBRA D0,@Repeat ; UNTIL (entire table has been copied)
-
- MOVEM.L (SP)+,D6-D7 ; RESTORE WORK REGISTERS
-
- BRA StatGood ; => return no error
-
-
-
-
- GetPage
- ;---------------------------------------------------------------------
- ;
- ; Return the number of pages in the specified mode
- ;
- ;---------------------------------------------------------------------
-
- MOVE csMode(A2),D1 ; get the mode
- BSR ChkMode ; check mode, get depth in D1
- BNE StatBad ; => not a valid mode
-
- MOVE.L dCtlStorage(A1),A0 ; get private storage pointer
- TST.B VRAM256K(A0) ; 512K or 256K?
- BNE.S @1 ; if TRUE, then 256K of RAM
- MOVEQ #4,D0 ; if FALSE, 512K vRAM (and 1 more page per mode)
- BRA.S @2
- @1 MOVEQ #3,D0 ; get one-bit page count
- @2 DIVU D1,D0 ; divide by depth
- ADD #1,D0 ; make it one based
- MOVE D0,csPage(A2) ; return page count
- BRA StatGood ; => return no error
-
-
-
- GetPageBase
- ;---------------------------------------------------------------------
- ;
- ; Return the base address for the specified page in the current mode
- ;
- ;---------------------------------------------------------------------
-
- MOVE.L dCtlStorage(A1),A3 ; get handle to our storage
- MOVE.L (A3),A3 ; get pointer to our storage
- MOVE saveMode(A3),D1 ; get the current mode
- BSR ChkMode ; convert to depth in D1
- MOVE.W csPage(A2),D0 ; get the requested page
- BSR ChkPage ; is the page valid?
- BNE StatBad ; => no, just return
-
- MOVE saveMode(A3),D1 ; get the current mode
- SUB #OneBitMode,D1 ; make it 0 based
- LEA ModeTbl,A0 ; point to tables
- MULU 4(A0,D1*8),D0 ; calc page * rowBytes
- MULU 6(A0,D1*8),D0 ; calc page * rowBytes * height
- MOVEQ #defmBaseOffset,D1 ; add offset for TFB
- ADD.L D1,D0 ; which doesn't use first long
- ADD.L dCtlDevBase(A1),D0 ; add base address for card
- MOVE.L D0,csBaseAddr(A2) ; return the base address
-
- BRA StatGood ; => return no error
-
-
- GetGray
- ;---------------------------------------------------------------------
- ;
- ; Return a boolean, set true if luminance mapping is on
- ;
- ;---------------------------------------------------------------------
-
- CLR csMode(A2) ; assume that grayFlag is false
- MOVE.L dCtlStorage(A1),A3 ; get handle to our storage
- MOVE.L (A3),A3 ; get pointer to our storage
- TST GFlags(A3) ; is luminance mapping on?
- BPL StatGood ; => no, return false
- MOVE.B #1,csMode(A2) ; else return true
- BRA StatGood ; => and return
-
-
- GetInterrupt
- ;---------------------------------------------------------------------
- ;
- ; Return a boolean in csMode, set true if VBL interrupts are disabled
- ;
- ;---------------------------------------------------------------------
-
- CLR csMode(A2) ; assume that grayFlag is false
- MOVE.L dCtlStorage(A1),A3 ; get handle to our storage
- MOVE.L (A3),A3 ; get pointer to our storage
- BTST #IntDisFlag,GFlags(A3) ; is luminance mapping on?
- BEQ StatGood ; => no, return false
- MOVE.B #1,csMode(A2) ; else return true
- BRA StatGood ; => and return
-
-
- GetGamma
- ;---------------------------------------------------------------------
- ;
- ; Return the handle to the current gamma table
- ;
- ;---------------------------------------------------------------------
-
- MOVE.L dCtlStorage(A1),A3 ; get handle to our storage
- MOVE.L (A3),A3 ; get pointer to our storage
- MOVE.L GammaPtr(A3),csGTable(A2) ; return the pointer to the structure
- BRA StatGood ; and return a good result
-
-
- ;
- ;=====================================================================
- ;
- ; Special.
- ;
- ;=====================================================================
-
-
- ;---------------------------------------------------------------------
- ;
- ; Wait for vertical blanking
- ;
- ; A1 = DCE POINTER
- ;---------------------------------------------------------------------
-
- WaitVSync
-
- IF NOT TFB1K THEN
-
- MOVEM.L A0/D0,-(SP) ;save work registers
- MOVE SR,-(SP) ;set disable interrupt disable up to level 2
- MOVE.W #$2200,SR ;
-
- ; Loop until Vertical Blanking signal
-
- MOVE (SP)+,SR ;RE-ENABLE CURSOR INTERRUPTS
- MOVEM.L (SP)+,A0/D0 ;restore work registers
- ENDIF
- RTS
-
- ;---------------------------------------------------------------------
- ;
- ; Exit from control or Status.
- ;
- ;---------------------------------------------------------------------
-
- ExitDrvr BTST #NoQueueBit,ioTrap(A0) ; no queue bit set?
- BEQ.S GoIODone ; => no, not immediate
- RTS ; otherwise, it was an immediate call
-
- GoIODone MOVE.L JIODone,A0 ; get the IODone address
- JMP (A0) ; invoke it
-
-
-
-
- ;=====================================================================
- ;
- ; Utilities
- ;
- ;=====================================================================
-
-
- ;---------------------------------------------------------------------
- ;
- ; CvtIndex
- ;
- ; Calculate the proper index for the hw dependent CLUT given a
- ; hw independent index. (for example: <0,1,2,3> => <$00,$40,$80,$C0>
- ;
- ; -> A1 : Ptr to the DCE.
- ; <- D6 : The Index Range (1,3,15 or 255).
- ; <- D7 : The Shift Constant (7,6,4 or 0).
- ;
- ;---------------------------------------------------------------------
-
- ; Save registers
- CvtIndex MOVEM.L A3/D0/D4,-(SP) ; Save registers
-
- ; Get the mode (D4). mode will be 1,2,4 or 8.
- MOVE.L dCtlStorage(A1),A3 ; D7 <- the mode (onebitmode, twobitmode,....)
- MOVE.L (A3),A3
- MOVE.W saveMode(A3),D7
- SUB.W #OneBitMode,D7 ; D7 <- (0,1,2 or 3)
- MOVEQ #1,D4 ; D4 <- 1 << D3 {ie. 1,2,4 or 8}
- LSL.W D7,D4
-
- ; Determine the index range (D6). Range will be in [0..n], we need to calculate n.
- MOVE.W D4,D0 ; D0 <- (0,1,3 or 7)
- SUBQ #1,D0
- MOVEQ #2,D6 ; D6 <- (2 << D0) - 1 {ie. 1,3,15,255}
- LSL.W D0,D6
- SUBQ #1,D6
-
- ; Determine the shift constant (D7). SC = (7,6,4 or 0).
- MOVEQ #8,D7 ; D7 <- (7,6,4 or 0)
- SUB.W D4,D7
-
- ; End
- MOVEM.L (SP)+,A3/D0/D4 ; Restore registers
- RTS
-
-
- ;---------------------------------------------------------------------
- ;
- ; ChkMode
- ;
- ; Maps the mode to a depth (1, 2, 4 or 8)
- ; Assumes DCE pointer in A1.
- ;
- ; -> D1: Mode
- ; <- D1: Depth
- ; D0: trashed
- ;
- ; Returns EQ if mode is valid.
-
- ChkMode SUB #OneBitMode,D1 ; make it 0 based
- BMI.S ModeBad ; =>bad mode, return
-
- CMP #3,D1 ; is it too big?
- BGT.S ModeBad ; =>yes, return
-
- MOVEQ #1,D0 ; get a one
- LSL D1,D0 ; convert to a depth
- MOVE D0,D1 ; and return in D1
-
- CMP.W #8,D1 ; requesting 8-Bit mode?
- BNE.S @1 ; 1,2,4 always OK
- MOVE.L A0,-(SP) ; save A0
- MOVE.L dCtlStorage(A1),A0 ; get handle to private storage
- MOVE.L (A0),A0 ; get pointer to private storage
- TST.B VRAM256K(A0) ; is there too little RAM?
- MOVE.L (SP)+,A0 ; restore register
- BNE.S ModeBad ; if TRUE, then return error
- @1
-
- ModeOK CMP.W D1,D1 ; get EQ
- ModeBad RTS ; EQ if valid depth
-
-
- ;---------------------------------------------------------------------
- ;
- ; ChkPage
- ;
- ; Checks to see if the page in D0 is valid for the depth in D1.
- ; Max page numbers are 4 for 1 bit mode; 2 for 2 bit mode; 1 for 4 bit mode;
- ; and 0 for 8 bit mode.
- ; Assumes DCE pointer in A1.
- ;
- ; -> D0: Page
- ; -> D1: Depth
- ;
- ; Returns EQ if page is valid.
-
- ChkPage MOVEM.L D2/A0,-(SP) ; save work registers
- MOVE.L dCtlStorage(A1),A0 ; get private storage handle
- MOVE.L (A0),A0 ; get pointer to private storage
- TST.B VRAM256K(A0) ; 512K or 256K?
- BNE.S @1 ; if TRUE, then 256K of RAM
- MOVEQ #4,D2 ; if FALSE, 512K vRAM (and 1 more page per mode)
- BRA.S @2
- @1 MOVEQ #3,D2 ; get max one bit page count
- @2 DIVU D1,D2 ; divide by depth
- CMP D2,D0 ; is page # too big?
- SGT D2 ; set flag if too big
- TST.B D2 ; and test condition
- MOVEM.L (SP)+,D2/A0 ; restore work registers
- RTS
-
-
- ;---------------------------------------------------------------------
- ; InitTFB initializes the TFB
- ; All Registers preserved
- ;---------------------------------------------------------------------
-
- TFBInit MOVEM.L D0/A0/A1,-(SP) ;save all regs
-
- ; Video card initialization
-
- MOVEM.L (SP)+,D0/A0/A1 ;restore all regs
- RTS ;init done
-
-
- TFBSetDepth
- ;---------------------------------------------------------------------
- ; SetDepth sets the TFB depth
- ; D1 contains the depth (1,2,4,8}
- ; A1 = DCE pointer
- ; A2 = parameter block pointer
- ; A3 = dCtlStorage pointer
- ; Preserves all registers
- ;---------------------------------------------------------------------
-
-
- MOVEM.L D0-D2/A0-A1,-(SP) ;save all regs
-
- ; save the new mode
-
- MOVE.W csMode(A2),saveMode(A3) ; save the mode
-
- ; Set the video card depth
-
- MOVEM.L (SP)+,D0-D2/A0-A1 ;restore all regs
- RTS ;return
-
- TFBSetPage
- ;---------------------------------------------------------------------
- ; Entry: D0 = Page # (0 based)
- ; A1 = DCE pointer
- ; A2 = parameter block pointer
- ; A3 = dCtlStorage pointer
- ;
- ; The base of a page is at dCtlDevBase + 4 + (page * RowBytes * height)
- ;
- ; All registers are preserved.
-
- MOVEM.L D0-D1/A0-A1,-(SP) ; save all registers
-
- MOVE D0,savePage(A3) ; save the page
- MOVE csMode(A2),D1 ; get the mode
- SUB #OneBitMode,D1 ; make it 0 based
- LEA ModeTbl,A0 ; point to tables
- MULU 4(A0,D1*8),D0 ; calc page * rowBytes
- MULU 6(A0,D1*8),D0 ; calc page * rowBytes * height
- MOVEQ #defmBaseOffset,D1 ; add offset for TFB
- ADD.L D1,D0 ; which doesn't use first long
- MOVE.L D0,D1 ; save offset to page in bytes
- MOVE.L dCtlDevBase(A1),A0 ; get base for device
- ADD.L A0,D0 ; add the slot's base address
- MOVE.L D0,saveBaseAddr(A3) ; save the base address
-
- ; Now set the hardware by writing the offset in longs to the proper registers.
-
- MOVEM.L (SP)+,D0-D1/A0-A1 ; restore all registers
- RTS ; and return
-
-
- GrayScreen
- ;---------------------------------------------------------------------
- ; D0 = Page
- ; A3 = dCtlStorage Ptr.
- ;
- ; All registers are preserved.
-
- MOVEM.L D0-D4/A0-A1,-(SP) ; save all registers
- MOVE csMode(A2),D1 ; get the mode
- SUB #OneBitMode,D1 ; make it 0 based
- CMP.W #3,D1 ; if 8-bit req, test for RAM
- BNE.S @1 ; 1,2,4 bit requests are always OK
- TST.B VRAM256K(A3) ; is there enough RAM?
- BNE.S GSDone ; if TRUE, then don't do anything
- @1 LEA ModeTbl,A1 ; point to tables
- MOVE.L 0(A1,D1*8),D0 ; D0 = the proper pattern
- MOVE 4(A1,D1*8),D4 ; D4 = rowbytes for the screen
- MOVE 6(A1,D1*8),D3 ; D3 = screen height
- SUBQ #1,D3 ; make it 0 based
- MOVE.L D0,D1 ; get inverse of pattern
- NOT.L D1 ; for alternate lines
-
- MOVE.L saveBaseAddr(A3),A1 ; point to the current page
- NxtRow1 MOVE.L A1,A0 ; get next row
- MOVE.W D4,D2 ; get bytes per row
- LSR #2,D2 ; get longs per row
- SUBQ #1,D2 ; make count 0 based
- NxtLong1 MOVE.L D0,(A0)+ ; write gray
- DBF D2,NxtLong1 ; for entire width of row
- EXG D0,D1 ; get inverse gray for next row
- ADD.W D4,A1 ; bump to next row
- DBF D3,NxtRow1 ; until no more rows
- GSDone
- MOVEM.L (SP)+,D0-D4/A0-A1 ; restore all registers
- RTS ; and return
-
-
- ; Mode info: Pattern,RowBytes,Height
-
- ModeTbl DC.W $AAAA,$AAAA,$0080,$01E0 ; one bit per pixel
- DC.W $CCCC,$CCCC,$0100,$01E0 ; two bit per pixel
- DC.W $F0F0,$F0F0,$0200,$01E0 ; four bit per pixel
- DC.W $FF00,$FF00,$0400,$01E0 ; eight bit per pixel
-
-
- ;-------------------------------------------------------------
- ; The Interrupt handler for TFB board
- ;-------------------------------------------------------------
- ; The interrupt Handler
- ; On entry A1 contains the slot base address
- ; D0-D3/A0-A3 have been preserved.
- BeginIH MOVE.L A1,A0 ; get screen base
- MOVE.L A1,D0 ; and save for later
- ADD.L #ClrVInt,A0 ; get offset to register
- CLR.B (A0) ; clear interrupt from card
-
- ; D0 = $Fssxxxxx
- ROL.L #8,D0 ; D0 <- $sxxxxxFs Convert the address into
- AND #$0F,D0 ; D0 <- $sxxx000s the slot number.
-
- MOVE.L JVBLTask,A0 ; call the VBL task manager
- JSR (A0) ; with slot # in D0
-
- MOVEQ #1,D0 ; signal that int was serviced
- RTS ; and return to caller
-
-